home *** CD-ROM | disk | FTP | other *** search
- go :- cls, display('***********'), nl, nl, tag(main), fail.
- go :- nl, display('*********** - ended.'), nl.
-
- main :- repeat,
- getwords(Words), compile(Words, Cmd), do(Cmd), fail.
-
- % READER and SCANNER
-
- getwords(Words) :- rdchsk(FirstCh), getwords(FirstCh, Words).
-
- getwords(Eoln, []) :- iseoln(Eoln), !.
- getwords(Noletter, Words) :- not letter(Noletter), !, rch,
- lastch(NextCh), getwords(NextCh, Words).
- getwords(Letter, [Word | Words]) :- absorb(Letter, String, NextCh),
- pname(Word, String), getwords(NextCh, Words).
-
- absorb(Noletter, [], Noletter) :- not letter(Noletter), !.
- absorb(Letter, [Small | Letters], NextCh) :- small(Letter, Small),
- rch, lastch(MiddleCh), absorb(MiddleCh, Letters, NextCh).
-
- small(Small, Small) :- smalletter(Small), !.
- small(Big, Small) :-
- ordchr(BOrd, Big), sum(BOrd, 32, SOrd), ordchr(SOrd, Small).
-
- % parse a command and execute it
-
- compile(WList, Cmd) :- phrase(command(Cmd), WList), !.
- compile(WList, _) :- display('Can''t compile " '), showlist(WList),
- display('".'), nl, fail.
-
- showlist([]) :- !.
- showlist([Word | Words]) :- display(Word), wch(' '), showlist(Words).
-
-
- do(Cmd) :- Cmd, !, display('OK.'), nl.
- do(_) :- display('I can''t !'), nl.
-
- %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
- command( assert(T) ) -->
- [Name1, 'is'], article, [Name2], !, { T =.. [Name2, Name1] }.
-
- command( assert( (Left :- Right) ) ) -->
- article, [Name1, 'is'], article, [Name2], !,
- { Left =.. [Name2, X], Right =.. [Name1, X] }.
-
- command( tagfail(main) ) --> [bye], !.
-
- command( (Term, display('Yes.'), nl) ; (display('I don''t know !'), nl) ) -->
- ['is', Name1], article, [Name2], !,
- { Term =.. [Name2, Name1] }.
-
- article --> [a], !.
- article --> [an].
-
- end.
-
-